-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.

module Wire.API.Routes.Internal.Brig
  ( API,
    BrigInternalClient,
    brigInternalClient,
    runBrigInternalClient,
    IStatusAPI,
    AccountAPI,
    MLSAPI,
    TeamsAPI,
    UserAPI,
    ClientAPI,
    AuthAPI,
    FederationRemotesAPI,
    EJPDRequest,
    ISearchIndexAPI,
    ProviderAPI,
    GetAccountConferenceCallingConfig,
    PutAccountConferenceCallingConfig,
    DeleteAccountConferenceCallingConfig,
    swaggerDoc,
    module Wire.API.Routes.Internal.Brig.EJPD,
    FoundInvitationCode (..),
  )
where

import Control.Lens ((.~))
import Data.Aeson (FromJSON, ToJSON)
import Data.Code qualified as Code
import Data.CommaSeparatedList
import Data.Domain (Domain)
import Data.Handle (Handle)
import Data.Id as Id
import Data.OpenApi (HasInfo (info), HasTitle (title), OpenApi)
import Data.OpenApi qualified as S
import Data.Qualified (Qualified)
import Data.Schema hiding (swaggerDoc)
import Data.Text qualified as Text
import GHC.TypeLits
import Imports hiding (head)
import Network.HTTP.Client qualified as HTTP
import Servant hiding (Handler, addHeader, respond)
import Servant.Client qualified as Servant
import Servant.Client.Core qualified as Servant
import Servant.OpenApi (HasOpenApi (toOpenApi))
import Servant.OpenApi.Internal.Orphans ()
import Util.Options
import Wire.API.Connection
import Wire.API.Error
import Wire.API.Error.Brig
import Wire.API.MLS.CipherSuite
import Wire.API.Routes.FederationDomainConfig
import Wire.API.Routes.Internal.Brig.Connection
import Wire.API.Routes.Internal.Brig.EJPD
import Wire.API.Routes.Internal.Brig.OAuth (OAuthAPI)
import Wire.API.Routes.Internal.Brig.SearchIndex (ISearchIndexAPI)
import Wire.API.Routes.Internal.Galley.TeamFeatureNoConfigMulti qualified as Multi
import Wire.API.Routes.Internal.LegalHold qualified as LegalHoldInternalAPI
import Wire.API.Routes.MultiVerb
import Wire.API.Routes.Named
import Wire.API.Routes.Public (ZUser)
import Wire.API.Team.Export (TeamExportUser)
import Wire.API.Team.Feature
import Wire.API.Team.Invitation (Invitation)
import Wire.API.Team.LegalHold.Internal
import Wire.API.Team.Size qualified as Teamsize
import Wire.API.User hiding (InvitationCode)
import Wire.API.User qualified as User
import Wire.API.User.Auth
import Wire.API.User.Auth.LegalHold
import Wire.API.User.Auth.ReAuth
import Wire.API.User.Auth.Sso
import Wire.API.User.Client
import Wire.API.User.RichInfo

type EJPDRequest =
  Summary
    "Identify users for law enforcement.  Wire has legal requirements to cooperate \
    \with the authorities.  The wire backend operations team uses this to answer \
    \identification requests manually.  It is our best-effort representation of the \
    \minimum required information we need to hand over about targets and (in some \
    \cases) their communication peers.  For more information, consult ejpd.admin.ch."
    :> "ejpd-request"
    :> QueryParam'
         [ Optional,
           Strict,
           Description "Also provide information about all contacts of the identified users"
         ]
         "include_contacts"
         Bool
    :> Servant.ReqBody '[Servant.JSON] EJPDRequestBody
    :> Post '[Servant.JSON] EJPDResponseBody

type GetAccountConferenceCallingConfig =
  Summary
    "Read cassandra field 'brig.user.feature_conference_calling'"
    :> "users"
    :> Capture "uid" UserId
    :> "features"
    :> "conferenceCalling"
    :> Get '[Servant.JSON] (Feature ConferenceCallingConfig)

type PutAccountConferenceCallingConfig =
  Summary
    "Write to cassandra field 'brig.user.feature_conference_calling'"
    :> "users"
    :> Capture "uid" UserId
    :> "features"
    :> "conferenceCalling"
    :> Servant.ReqBody '[Servant.JSON] (Feature ConferenceCallingConfig)
    :> Put '[Servant.JSON] NoContent

type DeleteAccountConferenceCallingConfig =
  Summary
    "Reset cassandra field 'brig.user.feature_conference_calling' to 'null'"
    :> "users"
    :> Capture "uid" UserId
    :> "features"
    :> "conferenceCalling"
    :> Delete '[Servant.JSON] NoContent

type GetAllConnectionsUnqualified =
  Summary "Get all connections of a given user"
    :> "users"
    :> "connections-status"
    :> ReqBody '[Servant.JSON] ConnectionsStatusRequest
    :> QueryParam'
         [ Optional,
           Strict,
           Description "Only returns connections with the given relation, if omitted, returns all connections"
         ]
         "filter"
         Relation
    :> Post '[Servant.JSON] [ConnectionStatus]

type GetAllConnections =
  Summary "Get all connections of a given user"
    :> "users"
    :> "connections-status"
    :> "v2"
    :> ReqBody '[Servant.JSON] ConnectionsStatusRequestV2
    :> Post '[Servant.JSON] [ConnectionStatusV2]

type AccountAPI =
  Named "get-account-conference-calling-config" GetAccountConferenceCallingConfig
    :<|> PutAccountConferenceCallingConfig
    :<|> DeleteAccountConferenceCallingConfig
    :<|> GetAllConnectionsUnqualified
    :<|> GetAllConnections
    :<|> Named
           "createUserNoVerify"
           -- This endpoint can lead to the following events being sent:
           -- - UserActivated event to created user, if it is a team invitation or user has an SSO ID
           -- - UserIdentityUpdated event to created user, if email or phone get activated
           ( "users"
               :> ReqBody '[Servant.JSON] NewUser
               :> MultiVerb 'POST '[Servant.JSON] RegisterInternalResponses (Either RegisterError SelfProfile)
           )
    :<|> Named
           "createUserNoVerifySpar"
           ( "users"
               :> "spar"
               :> ReqBody '[Servant.JSON] NewUserSpar
               :> MultiVerb 'POST '[Servant.JSON] CreateUserSparInternalResponses (Either CreateUserSparError SelfProfile)
           )
    :<|> Named
           "putSelfEmail"
           ( Summary
               "Internal email update and activation. Used in tests and in spar for validating emails \
               \obtained via scim or saml implicit user creation. If the `validate` query parameter is \
               \false or missing, only update the email and do not activate."
               :> ZUser
               :> "self"
               :> "email"
               :> ReqBody '[Servant.JSON] EmailUpdate
               :> QueryParam' [Optional, Strict, Description "whether to send validation email, or activate"] "validate" Bool
               :> MultiVerb
                    'PUT
                    '[Servant.JSON]
                    '[ Respond 202 "Update accepted and pending activation of the new email" (),
                       Respond 204 "No update, current and new email address are the same" ()
                     ]
                    ChangeEmailResponse
           )
    :<|> Named
           "iDeleteUser"
           ( Summary
               "This endpoint will lead to the following events being sent: UserDeleted event to all of \
               \its contacts, MemberLeave event to members for all conversations the user was in (via galley)"
               :> CanThrow 'UserNotFound
               :> "users"
               :> Capture "uid" UserId
               :> MultiVerb
                    'DELETE
                    '[Servant.JSON]
                    '[ Respond 200 "UserResponseAccountAlreadyDeleted" (),
                       Respond 202 "UserResponseAccountDeleted" ()
                     ]
                    DeleteUserResponse
           )
    :<|> Named
           "iPutUserStatus"
           ( -- FUTUREWORK: `CanThrow ... :>`
             "users"
               :> Capture "uid" UserId
               :> "status"
               :> ReqBody '[Servant.JSON] AccountStatusUpdate
               :> Put '[Servant.JSON] NoContent
           )
    :<|> Named
           "iGetUserStatus"
           ( CanThrow 'UserNotFound
               :> "users"
               :> Capture "uid" UserId
               :> "status"
               :> Get '[Servant.JSON] AccountStatusResp
           )
    :<|> Named
           "iGetUsersByVariousKeys"
           ( "users"
               :> QueryParam' [Optional, Strict] "ids" (CommaSeparatedList UserId)
               :> QueryParam' [Optional, Strict] "handles" (CommaSeparatedList Handle)
               :> QueryParam' [Optional, Strict] "email" (CommaSeparatedList EmailAddress) -- don't rename to `emails`, for backwards compat!
               :> QueryParam'
                    [ Optional,
                      Strict,
                      Description "Also return new accounts with team invitation pending"
                    ]
                    "includePendingInvitations"
                    Bool
               :> Get '[Servant.JSON] [User]
           )
    :<|> Named
           "iGetUserContacts"
           ( "users"
               :> Capture "uid" UserId
               :> "contacts"
               :> Get '[Servant.JSON] UserIds
           )
    :<|> Named
           "iGetUserActivationCode"
           ( "users"
               :> "activation-code"
               :> QueryParam' [Required, Strict] "email" EmailAddress
               :> Get '[Servant.JSON] GetActivationCodeResp
           )
    :<|> Named
           "iGetUserPasswordResetCode"
           ( "users"
               :> "password-reset-code"
               :> QueryParam' [Required, Strict] "email" EmailAddress
               :> Get '[Servant.JSON] GetPasswordResetCodeResp
           )
    :<|> Named
           "iRevokeIdentity"
           ( Summary "This endpoint can lead to the following events being sent: UserIdentityRemoved event to target user"
               :> "users"
               :> "revoke-identity"
               :> QueryParam' [Required, Strict] "email" EmailAddress
               :> Post '[Servant.JSON] NoContent
           )
    :<|> Named
           "iHeadBlacklist"
           ( "users"
               :> "blacklist"
               :> QueryParam' [Required, Strict] "email" EmailAddress
               :> MultiVerb
                    'GET
                    '[Servant.JSON]
                    '[ Respond 404 "Not blacklisted" (),
                       Respond 200 "Yes blacklisted" ()
                     ]
                    CheckBlacklistResponse
           )
    :<|> Named
           "iDeleteBlacklist"
           ( "users"
               :> "blacklist"
               :> QueryParam' [Required, Strict] "email" EmailAddress
               :> Delete '[Servant.JSON] NoContent
           )
    :<|> Named
           "iPostBlacklist"
           ( "users"
               :> "blacklist"
               :> QueryParam' [Required, Strict] "email" EmailAddress
               :> Post '[Servant.JSON] NoContent
           )
    :<|> Named
           "iPutUserSsoId"
           ( "users"
               :> Capture "uid" UserId
               :> "sso-id"
               :> ReqBody '[Servant.JSON] UserSSOId
               :> MultiVerb
                    'PUT
                    '[Servant.JSON]
                    '[ RespondEmpty 200 "UpdateSSOIdSuccess",
                       RespondEmpty 404 "UpdateSSOIdNotFound"
                     ]
                    UpdateSSOIdResponse
           )
    :<|> Named
           "iDeleteUserSsoId"
           ( "users"
               :> Capture "uid" UserId
               :> "sso-id"
               :> MultiVerb
                    'DELETE
                    '[Servant.JSON]
                    '[ RespondEmpty 200 "UpdateSSOIdSuccess",
                       RespondEmpty 404 "UpdateSSOIdNotFound"
                     ]
                    UpdateSSOIdResponse
           )
    :<|> Named
           "iPutManagedBy"
           ( "users"
               :> Capture "uid" UserId
               :> "managed-by"
               :> ReqBody '[Servant.JSON] ManagedByUpdate
               :> Put '[Servant.JSON] NoContent
           )
    :<|> Named
           "iPutRichInfo"
           ( "users"
               :> Capture "uid" UserId
               :> "rich-info"
               :> ReqBody '[Servant.JSON] RichInfoUpdate
               :> Put '[Servant.JSON] NoContent
           )
    :<|> Named
           "iPutHandle"
           ( "users"
               :> Capture "uid" UserId
               :> "handle"
               :> ReqBody '[Servant.JSON] HandleUpdate
               :> Put '[Servant.JSON] NoContent
           )
    :<|> Named
           "iPutUserName"
           ( "users"
               :> Capture "uid" UserId
               :> "name"
               :> ReqBody '[Servant.JSON] NameUpdate
               :> Put '[Servant.JSON] NoContent
           )
    :<|> Named
           "iGetRichInfo"
           ( "users"
               :> Capture "uid" UserId
               :> "rich-info"
               :> Get '[Servant.JSON] RichInfo
           )
    :<|> Named
           "iGetRichInfoMulti"
           ( "users"
               :> "rich-info"
               :> QueryParam' '[Optional, Strict] "ids" (CommaSeparatedList UserId)
               :> Get '[Servant.JSON] [(UserId, RichInfo)]
           )
    :<|> Named
           "iHeadHandle"
           ( CanThrow 'InvalidHandle
               :> "users"
               :> "handles"
               :> Capture "handle" Handle
               :> MultiVerb
                    'HEAD
                    '[Servant.JSON]
                    '[ RespondEmpty 200 "CheckHandleResponseFound",
                       RespondEmpty 404 "CheckHandleResponseNotFound"
                     ]
                    CheckHandleResponse
           )
    :<|> Named
           "iConnectionUpdate"
           ( "connections"
               :> "connection-update"
               :> ReqBody '[Servant.JSON] UpdateConnectionsInternal
               :> Put '[Servant.JSON] NoContent
           )
    :<|> Named
           "iListClients"
           ( "clients"
               :> ReqBody '[Servant.JSON] UserSet
               :> Post '[Servant.JSON] UserClients
           )
    :<|> Named
           "iListClientsFull"
           ( "clients"
               :> "full"
               :> ReqBody '[Servant.JSON] UserSet
               :> Post '[Servant.JSON] UserClientsFull
           )
    :<|> Named
           "iAddClient"
           ( Summary
               "This endpoint can lead to the following events being sent: ClientAdded event to the user; \
               \ClientRemoved event to the user, if removing old clients due to max number of clients; \
               \UserLegalHoldEnabled event to contacts of the user, if client type is legalhold."
               :> "clients"
               :> Capture "uid" UserId
               :> QueryParam' [Optional, Strict] "skip_reauth" Bool
               :> ReqBody '[Servant.JSON] NewClient
               :> Header' [Optional, Strict] "Z-Connection" ConnId
               :> Verb 'POST 201 '[Servant.JSON] Client
           )
    :<|> Named
           "iLegalholdAddClient"
           ( Summary
               "This endpoint can lead to the following events being sent: \
               \LegalHoldClientRequested event to contacts of the user"
               :> "clients"
               :> "legalhold"
               :> Capture "uid" UserId
               :> "request"
               :> ReqBody '[Servant.JSON] LegalHoldClientRequest
               :> Post '[Servant.JSON] NoContent
           )
    :<|> Named
           "iLegalholdDeleteClient"
           ( Summary
               "This endpoint can lead to the following events being sent: \
               \ClientRemoved event to the user; UserLegalHoldDisabled event \
               \to contacts of the user"
               :> "clients"
               :> "legalhold"
               :> Capture "uid" UserId
               :> Delete '[Servant.JSON] NoContent
           )

-- | The missing ref is implicit by the capture
data NewKeyPackageRef = NewKeyPackageRef
  { NewKeyPackageRef -> Qualified UserId
nkprUserId :: Qualified UserId,
    NewKeyPackageRef -> ClientId
nkprClientId :: ClientId,
    NewKeyPackageRef -> Qualified ConvId
nkprConversation :: Qualified ConvId
  }
  deriving stock (NewKeyPackageRef -> NewKeyPackageRef -> Bool
(NewKeyPackageRef -> NewKeyPackageRef -> Bool)
-> (NewKeyPackageRef -> NewKeyPackageRef -> Bool)
-> Eq NewKeyPackageRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NewKeyPackageRef -> NewKeyPackageRef -> Bool
== :: NewKeyPackageRef -> NewKeyPackageRef -> Bool
$c/= :: NewKeyPackageRef -> NewKeyPackageRef -> Bool
/= :: NewKeyPackageRef -> NewKeyPackageRef -> Bool
Eq, Int -> NewKeyPackageRef -> ShowS
[NewKeyPackageRef] -> ShowS
NewKeyPackageRef -> String
(Int -> NewKeyPackageRef -> ShowS)
-> (NewKeyPackageRef -> String)
-> ([NewKeyPackageRef] -> ShowS)
-> Show NewKeyPackageRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NewKeyPackageRef -> ShowS
showsPrec :: Int -> NewKeyPackageRef -> ShowS
$cshow :: NewKeyPackageRef -> String
show :: NewKeyPackageRef -> String
$cshowList :: [NewKeyPackageRef] -> ShowS
showList :: [NewKeyPackageRef] -> ShowS
Show, (forall x. NewKeyPackageRef -> Rep NewKeyPackageRef x)
-> (forall x. Rep NewKeyPackageRef x -> NewKeyPackageRef)
-> Generic NewKeyPackageRef
forall x. Rep NewKeyPackageRef x -> NewKeyPackageRef
forall x. NewKeyPackageRef -> Rep NewKeyPackageRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NewKeyPackageRef -> Rep NewKeyPackageRef x
from :: forall x. NewKeyPackageRef -> Rep NewKeyPackageRef x
$cto :: forall x. Rep NewKeyPackageRef x -> NewKeyPackageRef
to :: forall x. Rep NewKeyPackageRef x -> NewKeyPackageRef
Generic)
  deriving ([NewKeyPackageRef] -> Value
[NewKeyPackageRef] -> Encoding
NewKeyPackageRef -> Value
NewKeyPackageRef -> Encoding
(NewKeyPackageRef -> Value)
-> (NewKeyPackageRef -> Encoding)
-> ([NewKeyPackageRef] -> Value)
-> ([NewKeyPackageRef] -> Encoding)
-> ToJSON NewKeyPackageRef
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: NewKeyPackageRef -> Value
toJSON :: NewKeyPackageRef -> Value
$ctoEncoding :: NewKeyPackageRef -> Encoding
toEncoding :: NewKeyPackageRef -> Encoding
$ctoJSONList :: [NewKeyPackageRef] -> Value
toJSONList :: [NewKeyPackageRef] -> Value
$ctoEncodingList :: [NewKeyPackageRef] -> Encoding
toEncodingList :: [NewKeyPackageRef] -> Encoding
ToJSON, Value -> Parser [NewKeyPackageRef]
Value -> Parser NewKeyPackageRef
(Value -> Parser NewKeyPackageRef)
-> (Value -> Parser [NewKeyPackageRef])
-> FromJSON NewKeyPackageRef
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser NewKeyPackageRef
parseJSON :: Value -> Parser NewKeyPackageRef
$cparseJSONList :: Value -> Parser [NewKeyPackageRef]
parseJSONList :: Value -> Parser [NewKeyPackageRef]
FromJSON, Typeable NewKeyPackageRef
Typeable NewKeyPackageRef =>
(Proxy NewKeyPackageRef
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema NewKeyPackageRef
Proxy NewKeyPackageRef -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy NewKeyPackageRef -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy NewKeyPackageRef -> Declare (Definitions Schema) NamedSchema
S.ToSchema) via (Schema NewKeyPackageRef)

instance ToSchema NewKeyPackageRef where
  schema :: ValueSchema NamedSwaggerDoc NewKeyPackageRef
schema =
    Text
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef NewKeyPackageRef
-> ValueSchema NamedSwaggerDoc NewKeyPackageRef
forall doc doc' a b.
HasObject doc doc' =>
Text
-> SchemaP doc Object [Pair] a b -> SchemaP doc' Value Value a b
object Text
"NewKeyPackageRef" (SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef NewKeyPackageRef
 -> ValueSchema NamedSwaggerDoc NewKeyPackageRef)
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef NewKeyPackageRef
-> ValueSchema NamedSwaggerDoc NewKeyPackageRef
forall a b. (a -> b) -> a -> b
$
      Qualified UserId
-> ClientId -> Qualified ConvId -> NewKeyPackageRef
NewKeyPackageRef
        (Qualified UserId
 -> ClientId -> Qualified ConvId -> NewKeyPackageRef)
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef (Qualified UserId)
-> SchemaP
     SwaggerDoc
     Object
     [Pair]
     NewKeyPackageRef
     (ClientId -> Qualified ConvId -> NewKeyPackageRef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NewKeyPackageRef -> Qualified UserId
nkprUserId (NewKeyPackageRef -> Qualified UserId)
-> SchemaP
     SwaggerDoc Object [Pair] (Qualified UserId) (Qualified UserId)
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef (Qualified UserId)
forall (p :: * -> * -> *) a a' b.
Profunctor p =>
(a -> a') -> p a' b -> p a b
.= Text
-> SchemaP
     NamedSwaggerDoc Value Value (Qualified UserId) (Qualified UserId)
-> SchemaP
     SwaggerDoc Object [Pair] (Qualified UserId) (Qualified UserId)
forall doc' doc a b.
HasField doc' doc =>
Text
-> SchemaP doc' Value Value a b -> SchemaP doc Object [Pair] a b
field Text
"user_id" SchemaP
  NamedSwaggerDoc Value Value (Qualified UserId) (Qualified UserId)
forall a. ToSchema a => ValueSchema NamedSwaggerDoc a
schema
        SchemaP
  SwaggerDoc
  Object
  [Pair]
  NewKeyPackageRef
  (ClientId -> Qualified ConvId -> NewKeyPackageRef)
-> SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef ClientId
-> SchemaP
     SwaggerDoc
     Object
     [Pair]
     NewKeyPackageRef
     (Qualified ConvId -> NewKeyPackageRef)
forall a b.
SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef (a -> b)
-> SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef a
-> SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NewKeyPackageRef -> ClientId
nkprClientId (NewKeyPackageRef -> ClientId)
-> SchemaP SwaggerDoc Object [Pair] ClientId ClientId
-> SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef ClientId
forall (p :: * -> * -> *) a a' b.
Profunctor p =>
(a -> a') -> p a' b -> p a b
.= Text
-> SchemaP NamedSwaggerDoc Value Value ClientId ClientId
-> SchemaP SwaggerDoc Object [Pair] ClientId ClientId
forall doc' doc a b.
HasField doc' doc =>
Text
-> SchemaP doc' Value Value a b -> SchemaP doc Object [Pair] a b
field Text
"client_id" SchemaP NamedSwaggerDoc Value Value ClientId ClientId
forall a. ToSchema a => ValueSchema NamedSwaggerDoc a
schema
        SchemaP
  SwaggerDoc
  Object
  [Pair]
  NewKeyPackageRef
  (Qualified ConvId -> NewKeyPackageRef)
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef (Qualified ConvId)
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef NewKeyPackageRef
forall a b.
SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef (a -> b)
-> SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef a
-> SchemaP SwaggerDoc Object [Pair] NewKeyPackageRef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NewKeyPackageRef -> Qualified ConvId
nkprConversation (NewKeyPackageRef -> Qualified ConvId)
-> SchemaP
     SwaggerDoc Object [Pair] (Qualified ConvId) (Qualified ConvId)
-> SchemaP
     SwaggerDoc Object [Pair] NewKeyPackageRef (Qualified ConvId)
forall (p :: * -> * -> *) a a' b.
Profunctor p =>
(a -> a') -> p a' b -> p a b
.= Text
-> SchemaP
     NamedSwaggerDoc Value Value (Qualified ConvId) (Qualified ConvId)
-> SchemaP
     SwaggerDoc Object [Pair] (Qualified ConvId) (Qualified ConvId)
forall doc' doc a b.
HasField doc' doc =>
Text
-> SchemaP doc' Value Value a b -> SchemaP doc Object [Pair] a b
field Text
"conversation" SchemaP
  NamedSwaggerDoc Value Value (Qualified ConvId) (Qualified ConvId)
forall a. ToSchema a => ValueSchema NamedSwaggerDoc a
schema

type MLSAPI = "mls" :> GetMLSClients

type GetMLSClients =
  Summary "Return all clients and all MLS-capable clients of a user"
    :> "clients"
    :> CanThrow 'UserNotFound
    :> Capture "user" UserId
    :> QueryParam' '[Required, Strict] "ciphersuite" CipherSuite
    :> MultiVerb1
         'GET
         '[Servant.JSON]
         (Respond 200 "MLS clients" (Set ClientInfo))

type GetVerificationCode =
  Summary "Get verification code for a given email and action"
    :> "users"
    :> Capture "uid" UserId
    :> "verification-code"
    :> Capture "action" VerificationAction
    :> Get '[Servant.JSON] (Maybe Code.Value)

type API =
  "i"
    :> ( IStatusAPI
           :<|> EJPDRequest
           :<|> AccountAPI
           :<|> MLSAPI
           :<|> GetVerificationCode
           :<|> TeamsAPI
           :<|> UserAPI
           :<|> ClientAPI
           :<|> AuthAPI
           :<|> OAuthAPI
           :<|> ISearchIndexAPI
           :<|> FederationRemotesAPI
           :<|> ProviderAPI
       )

type IStatusAPI =
  Named
    "get-status"
    ( Summary "do nothing, just check liveness (NB: this works for both get, head)"
        :> "status"
        :> Get '[Servant.JSON] NoContent
    )

type TeamsAPI =
  Named
    "updateSearchVisibilityInbound"
    ( "teams"
        :> ReqBody '[Servant.JSON] (Multi.TeamStatus SearchVisibilityInboundConfig)
        :> Post '[Servant.JSON] ()
    )
    :<|> InvitationByEmail
    :<|> InvitationCode
    :<|> SuspendTeam
    :<|> UnsuspendTeam
    :<|> TeamSize
    :<|> TeamInvitations

type InvitationByEmail =
  Named
    "get-invitation-by-email"
    ( "teams"
        :> "invitations"
        :> "by-email"
        :> QueryParam' [Required, Strict] "email" EmailAddress
        :> Get '[Servant.JSON] Invitation
    )

type InvitationCode =
  Named
    "get-invitation-code"
    ( "teams"
        :> "invitation-code"
        :> QueryParam' [Required, Strict] "team" TeamId
        :> QueryParam' [Required, Strict] "invitation_id" InvitationId
        :> Get '[Servant.JSON] FoundInvitationCode
    )

newtype FoundInvitationCode = FoundInvitationCode {FoundInvitationCode -> InvitationCode
getFoundInvitationCode :: User.InvitationCode}
  deriving stock (FoundInvitationCode -> FoundInvitationCode -> Bool
(FoundInvitationCode -> FoundInvitationCode -> Bool)
-> (FoundInvitationCode -> FoundInvitationCode -> Bool)
-> Eq FoundInvitationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FoundInvitationCode -> FoundInvitationCode -> Bool
== :: FoundInvitationCode -> FoundInvitationCode -> Bool
$c/= :: FoundInvitationCode -> FoundInvitationCode -> Bool
/= :: FoundInvitationCode -> FoundInvitationCode -> Bool
Eq, Int -> FoundInvitationCode -> ShowS
[FoundInvitationCode] -> ShowS
FoundInvitationCode -> String
(Int -> FoundInvitationCode -> ShowS)
-> (FoundInvitationCode -> String)
-> ([FoundInvitationCode] -> ShowS)
-> Show FoundInvitationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FoundInvitationCode -> ShowS
showsPrec :: Int -> FoundInvitationCode -> ShowS
$cshow :: FoundInvitationCode -> String
show :: FoundInvitationCode -> String
$cshowList :: [FoundInvitationCode] -> ShowS
showList :: [FoundInvitationCode] -> ShowS
Show, (forall x. FoundInvitationCode -> Rep FoundInvitationCode x)
-> (forall x. Rep FoundInvitationCode x -> FoundInvitationCode)
-> Generic FoundInvitationCode
forall x. Rep FoundInvitationCode x -> FoundInvitationCode
forall x. FoundInvitationCode -> Rep FoundInvitationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FoundInvitationCode -> Rep FoundInvitationCode x
from :: forall x. FoundInvitationCode -> Rep FoundInvitationCode x
$cto :: forall x. Rep FoundInvitationCode x -> FoundInvitationCode
to :: forall x. Rep FoundInvitationCode x -> FoundInvitationCode
Generic)
  deriving (Value -> Parser [FoundInvitationCode]
Value -> Parser FoundInvitationCode
(Value -> Parser FoundInvitationCode)
-> (Value -> Parser [FoundInvitationCode])
-> FromJSON FoundInvitationCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser FoundInvitationCode
parseJSON :: Value -> Parser FoundInvitationCode
$cparseJSONList :: Value -> Parser [FoundInvitationCode]
parseJSONList :: Value -> Parser [FoundInvitationCode]
FromJSON, [FoundInvitationCode] -> Value
[FoundInvitationCode] -> Encoding
FoundInvitationCode -> Value
FoundInvitationCode -> Encoding
(FoundInvitationCode -> Value)
-> (FoundInvitationCode -> Encoding)
-> ([FoundInvitationCode] -> Value)
-> ([FoundInvitationCode] -> Encoding)
-> ToJSON FoundInvitationCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: FoundInvitationCode -> Value
toJSON :: FoundInvitationCode -> Value
$ctoEncoding :: FoundInvitationCode -> Encoding
toEncoding :: FoundInvitationCode -> Encoding
$ctoJSONList :: [FoundInvitationCode] -> Value
toJSONList :: [FoundInvitationCode] -> Value
$ctoEncodingList :: [FoundInvitationCode] -> Encoding
toEncodingList :: [FoundInvitationCode] -> Encoding
ToJSON, Typeable FoundInvitationCode
Typeable FoundInvitationCode =>
(Proxy FoundInvitationCode
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema FoundInvitationCode
Proxy FoundInvitationCode
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy FoundInvitationCode
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy FoundInvitationCode
-> Declare (Definitions Schema) NamedSchema
S.ToSchema) via (Schema FoundInvitationCode)

instance ToSchema FoundInvitationCode where
  schema :: ValueSchema NamedSwaggerDoc FoundInvitationCode
schema =
    InvitationCode -> FoundInvitationCode
FoundInvitationCode
      (InvitationCode -> FoundInvitationCode)
-> SchemaP
     NamedSwaggerDoc Value Value FoundInvitationCode InvitationCode
-> ValueSchema NamedSwaggerDoc FoundInvitationCode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FoundInvitationCode -> InvitationCode
getFoundInvitationCode (FoundInvitationCode -> InvitationCode)
-> SchemaP
     NamedSwaggerDoc Value Value InvitationCode InvitationCode
-> SchemaP
     NamedSwaggerDoc Value Value FoundInvitationCode InvitationCode
forall (p :: * -> * -> *) a a' b.
Profunctor p =>
(a -> a') -> p a' b -> p a b
.= Text
-> SchemaP SwaggerDoc Object [Pair] InvitationCode InvitationCode
-> SchemaP
     NamedSwaggerDoc Value Value InvitationCode InvitationCode
forall doc doc' a b.
HasObject doc doc' =>
Text
-> SchemaP doc Object [Pair] a b -> SchemaP doc' Value Value a b
object Text
"FoundInvitationCode" (Text
-> SchemaP
     NamedSwaggerDoc Value Value InvitationCode InvitationCode
-> SchemaP SwaggerDoc Object [Pair] InvitationCode InvitationCode
forall doc' doc a b.
HasField doc' doc =>
Text
-> SchemaP doc' Value Value a b -> SchemaP doc Object [Pair] a b
field Text
"code" (forall a. ToSchema a => ValueSchema NamedSwaggerDoc a
schema @User.InvitationCode))

type SuspendTeam =
  Named
    "suspend-team"
    ( "teams"
        :> Capture "tid" TeamId
        :> "suspend"
        :> Post
             '[Servant.JSON]
             NoContent
    )

type UnsuspendTeam =
  Named
    "unsuspend-team"
    ( "teams"
        :> Capture "tid" TeamId
        :> "unsuspend"
        :> Post
             '[Servant.JSON]
             NoContent
    )

type TeamSize =
  Named
    "team-size"
    ( "teams"
        :> Capture "tid" TeamId
        :> "size"
        :> Get '[JSON] Teamsize.TeamSize
    )

type TeamInvitations =
  Named
    "create-invitations-via-scim"
    ( "teams"
        :> Capture "tid" TeamId
        :> "invitations"
        :> Servant.ReqBody '[JSON] NewUserScimInvitation
        :> Post '[JSON] User
    )

type UserAPI =
  UpdateUserLocale
    :<|> DeleteUserLocale
    :<|> GetDefaultLocale
    :<|> Named
           "get-user-export-data"
           ( Summary "Get user export data"
               :> "users"
               :> Capture "uid" UserId
               :> "export-data"
               :> MultiVerb1 'GET '[JSON] (Respond 200 "User export data" (Maybe TeamExportUser))
           )

type UpdateUserLocale =
  Summary
    "Set the user's locale"
    :> "users"
    :> Capture "uid" UserId
    :> "locale"
    :> ReqBody '[Servant.JSON] LocaleUpdate
    :> Put '[Servant.JSON] LocaleUpdate

type DeleteUserLocale =
  Summary
    "Delete the user's locale"
    :> "users"
    :> Capture "uid" UserId
    :> "locale"
    :> Delete '[Servant.JSON] NoContent

type GetDefaultLocale =
  Summary "Get the default locale"
    :> "users"
    :> "locale"
    :> Get '[Servant.JSON] LocaleUpdate

type ClientAPI =
  Named
    "update-client-last-active"
    ( Summary "Update last_active field of a client"
        :> "clients"
        :> Capture "uid" UserId
        :> Capture "client" ClientId
        :> "activity"
        :> MultiVerb1 'POST '[Servant.JSON] (RespondEmpty 200 "OK")
    )

type AuthAPI =
  Named
    "legalhold-login"
    ( "legalhold-login"
        :> ReqBody '[JSON] LegalHoldLogin
        :> MultiVerb1 'POST '[JSON] TokenResponse
    )
    :<|> Named
           "sso-login"
           ( "sso-login"
               :> ReqBody '[JSON] SsoLogin
               :> QueryParam' [Optional, Strict] "persist" Bool
               :> MultiVerb1 'POST '[JSON] TokenResponse
           )
    :<|> Named
           "login-code"
           ( "users"
               :> "login-code"
               :> QueryParam' [Required, Strict] "phone" Phone
               :> MultiVerb1 'GET '[JSON] (Respond 200 "Login code" PendingLoginCode)
           )
    :<|> Named
           "reauthenticate"
           ( "users"
               :> Capture "uid" UserId
               :> "reauthenticate"
               :> ReqBody '[JSON] ReAuthUser
               :> MultiVerb1 'GET '[JSON] (RespondEmpty 200 "OK")
           )

-- | This is located in brig, not in federator, because brig has a cassandra instance.  This
-- is not ideal, and other services could keep their local in-ram copy of this table up to date
-- via rabbitmq, but FUTUREWORK.
type FederationRemotesAPI =
  Named
    "add-federation-remotes"
    ( Description FederationRemotesAPIDescription
        :> "federation"
        :> "remotes"
        :> ReqBody '[JSON] FederationDomainConfig
        :> Post '[JSON] ()
    )
    :<|> Named
           "get-federation-remotes"
           ( Description FederationRemotesAPIDescription
               :> "federation"
               :> "remotes"
               :> Get '[JSON] FederationDomainConfigs
           )
    :<|> Named
           "update-federation-remotes"
           ( Description FederationRemotesAPIDescription
               :> "federation"
               :> "remotes"
               :> Capture "domain" Domain
               :> ReqBody '[JSON] FederationDomainConfig
               :> Put '[JSON] ()
           )
    :<|> Named
           "add-federation-remote-team"
           ( Description
               "Add a remote team to the list of teams that are allowed to federate with our domain"
               :> "federation"
               :> "remotes"
               :> Capture "domain" Domain
               :> "teams"
               :> ReqBody '[JSON] FederationRemoteTeam
               :> Post '[JSON] ()
           )
    :<|> Named
           "get-federation-remote-teams"
           ( Description
               "Get a list of teams from a remote domain that our backend is allowed to federate with."
               :> "federation"
               :> "remotes"
               :> Capture "domain" Domain
               :> "teams"
               :> Get '[JSON] [FederationRemoteTeam]
           )
    :<|> Named
           "delete-federation-remote-team"
           ( Description
               "Remove a remote team from the list of teams that are allowed to federate with our domain"
               :> "federation"
               :> "remotes"
               :> Capture "domain" Domain
               :> "teams"
               :> Capture "team" TeamId
               :> Delete '[JSON] ()
           )

type ProviderAPI =
  ( Named
      "get-provider-activation-code"
      ( Summary "Retrieve activation code via api instead of email (for testing only)"
          :> "provider"
          :> "activation-code"
          :> QueryParam' '[Required, Strict] "email" EmailAddress
          :> MultiVerb1 'GET '[JSON] (Respond 200 "" Code.KeyValuePair)
      )
  )

type FederationRemotesAPIDescription =
  "See https://docs.wire.com/understand/federation/backend-communication.html#configuring-remote-connections for background. "

swaggerDoc :: OpenApi
swaggerDoc :: OpenApi
swaggerDoc =
  OpenApi
brigSwaggerDoc
    OpenApi -> OpenApi -> OpenApi
forall a. Semigroup a => a -> a -> a
<> OpenApi
LegalHoldInternalAPI.swaggerDoc

brigSwaggerDoc :: OpenApi
brigSwaggerDoc :: OpenApi
brigSwaggerDoc =
  ( Proxy
  ("i"
   :> (IStatusAPI
       :<|> (EJPDRequest
             :<|> ((Named
                      "get-account-conference-calling-config"
                      GetAccountConferenceCallingConfig
                    :<|> (PutAccountConferenceCallingConfig
                          :<|> (DeleteAccountConferenceCallingConfig
                                :<|> (GetAllConnectionsUnqualified
                                      :<|> (GetAllConnections
                                            :<|> (Named
                                                    "createUserNoVerify"
                                                    ("users"
                                                     :> (ReqBody '[JSON] NewUser
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              '[ErrorResponse 'AllowlistError,
                                                                ErrorResponse
                                                                  'InvalidInvitationCode,
                                                                ErrorResponse 'MissingIdentity,
                                                                ErrorResponse 'UserKeyExists,
                                                                ErrorResponse
                                                                  'InvalidActivationCodeWrongUser,
                                                                ErrorResponse
                                                                  'InvalidActivationCodeWrongCode,
                                                                ErrorResponse 'InvalidEmail,
                                                                ErrorResponse 'InvalidPhone,
                                                                ErrorResponse 'BlacklistedEmail,
                                                                ErrorResponse 'TooManyTeamMembers,
                                                                ErrorResponse
                                                                  'UserCreationRestricted,
                                                                WithHeaders
                                                                  '[DescHeader
                                                                      "Location" "UserId" UserId]
                                                                  SelfProfile
                                                                  (Respond
                                                                     201
                                                                     "User created and pending activation"
                                                                     SelfProfile)]
                                                              (Either RegisterError SelfProfile)))
                                                  :<|> (Named
                                                          "createUserNoVerifySpar"
                                                          ("users"
                                                           :> ("spar"
                                                               :> (ReqBody '[JSON] NewUserSpar
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[ErrorResponse
                                                                            'AllowlistError,
                                                                          ErrorResponse
                                                                            'InvalidInvitationCode,
                                                                          ErrorResponse
                                                                            'MissingIdentity,
                                                                          ErrorResponse
                                                                            'UserKeyExists,
                                                                          ErrorResponse
                                                                            'InvalidActivationCodeWrongUser,
                                                                          ErrorResponse
                                                                            'InvalidActivationCodeWrongCode,
                                                                          ErrorResponse
                                                                            'InvalidEmail,
                                                                          ErrorResponse
                                                                            'InvalidPhone,
                                                                          ErrorResponse
                                                                            'BlacklistedEmail,
                                                                          ErrorResponse
                                                                            'TooManyTeamMembers,
                                                                          ErrorResponse
                                                                            'UserCreationRestricted,
                                                                          ErrorResponse 'NoIdentity,
                                                                          ErrorResponse
                                                                            'HandleExists,
                                                                          ErrorResponse
                                                                            'InvalidHandle,
                                                                          ErrorResponse
                                                                            'HandleManagedByScim,
                                                                          WithHeaders
                                                                            '[DescHeader
                                                                                "Location"
                                                                                "UserId"
                                                                                UserId]
                                                                            SelfProfile
                                                                            (Respond
                                                                               201
                                                                               "User created and pending activation"
                                                                               SelfProfile)]
                                                                        (Either
                                                                           CreateUserSparError
                                                                           SelfProfile))))
                                                        :<|> (Named
                                                                "putSelfEmail"
                                                                (Summary
                                                                   "Internal email update and activation. Used in tests and in spar for validating emails obtained via scim or saml implicit user creation. If the `validate` query parameter is false or missing, only update the email and do not activate."
                                                                 :> (ZUser
                                                                     :> ("self"
                                                                         :> ("email"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   EmailUpdate
                                                                                 :> (QueryParam'
                                                                                       '[Optional,
                                                                                         Strict,
                                                                                         Description
                                                                                           "whether to send validation email, or activate"]
                                                                                       "validate"
                                                                                       Bool
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          '[Respond
                                                                                              202
                                                                                              "Update accepted and pending activation of the new email"
                                                                                              (),
                                                                                            Respond
                                                                                              204
                                                                                              "No update, current and new email address are the same"
                                                                                              ()]
                                                                                          ChangeEmailResponse))))))
                                                              :<|> (Named
                                                                      "iDeleteUser"
                                                                      (Summary
                                                                         "This endpoint will lead to the following events being sent: UserDeleted event to all of its contacts, MemberLeave event to members for all conversations the user was in (via galley)"
                                                                       :> (CanThrow 'UserNotFound
                                                                           :> ("users"
                                                                               :> (Capture
                                                                                     "uid" UserId
                                                                                   :> MultiVerb
                                                                                        'DELETE
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "UserResponseAccountAlreadyDeleted"
                                                                                            (),
                                                                                          Respond
                                                                                            202
                                                                                            "UserResponseAccountDeleted"
                                                                                            ()]
                                                                                        DeleteUserResponse))))
                                                                    :<|> (Named
                                                                            "iPutUserStatus"
                                                                            ("users"
                                                                             :> (Capture
                                                                                   "uid" UserId
                                                                                 :> ("status"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           AccountStatusUpdate
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              NoContent))))
                                                                          :<|> (Named
                                                                                  "iGetUserStatus"
                                                                                  (CanThrow
                                                                                     'UserNotFound
                                                                                   :> ("users"
                                                                                       :> (Capture
                                                                                             "uid"
                                                                                             UserId
                                                                                           :> ("status"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    AccountStatusResp))))
                                                                                :<|> (Named
                                                                                        "iGetUsersByVariousKeys"
                                                                                        ("users"
                                                                                         :> (QueryParam'
                                                                                               '[Optional,
                                                                                                 Strict]
                                                                                               "ids"
                                                                                               (CommaSeparatedList
                                                                                                  UserId)
                                                                                             :> (QueryParam'
                                                                                                   '[Optional,
                                                                                                     Strict]
                                                                                                   "handles"
                                                                                                   (CommaSeparatedList
                                                                                                      Handle)
                                                                                                 :> (QueryParam'
                                                                                                       '[Optional,
                                                                                                         Strict]
                                                                                                       "email"
                                                                                                       (CommaSeparatedList
                                                                                                          EmailAddress)
                                                                                                     :> (QueryParam'
                                                                                                           '[Optional,
                                                                                                             Strict,
                                                                                                             Description
                                                                                                               "Also return new accounts with team invitation pending"]
                                                                                                           "includePendingInvitations"
                                                                                                           Bool
                                                                                                         :> Get
                                                                                                              '[JSON]
                                                                                                              [User])))))
                                                                                      :<|> (Named
                                                                                              "iGetUserContacts"
                                                                                              ("users"
                                                                                               :> (Capture
                                                                                                     "uid"
                                                                                                     UserId
                                                                                                   :> ("contacts"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            UserIds)))
                                                                                            :<|> (Named
                                                                                                    "iGetUserActivationCode"
                                                                                                    ("users"
                                                                                                     :> ("activation-code"
                                                                                                         :> (QueryParam'
                                                                                                               '[Required,
                                                                                                                 Strict]
                                                                                                               "email"
                                                                                                               EmailAddress
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  GetActivationCodeResp)))
                                                                                                  :<|> (Named
                                                                                                          "iGetUserPasswordResetCode"
                                                                                                          ("users"
                                                                                                           :> ("password-reset-code"
                                                                                                               :> (QueryParam'
                                                                                                                     '[Required,
                                                                                                                       Strict]
                                                                                                                     "email"
                                                                                                                     EmailAddress
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        GetPasswordResetCodeResp)))
                                                                                                        :<|> (Named
                                                                                                                "iRevokeIdentity"
                                                                                                                (Summary
                                                                                                                   "This endpoint can lead to the following events being sent: UserIdentityRemoved event to target user"
                                                                                                                 :> ("users"
                                                                                                                     :> ("revoke-identity"
                                                                                                                         :> (QueryParam'
                                                                                                                               '[Required,
                                                                                                                                 Strict]
                                                                                                                               "email"
                                                                                                                               EmailAddress
                                                                                                                             :> Post
                                                                                                                                  '[JSON]
                                                                                                                                  NoContent))))
                                                                                                              :<|> (Named
                                                                                                                      "iHeadBlacklist"
                                                                                                                      ("users"
                                                                                                                       :> ("blacklist"
                                                                                                                           :> (QueryParam'
                                                                                                                                 '[Required,
                                                                                                                                   Strict]
                                                                                                                                 "email"
                                                                                                                                 EmailAddress
                                                                                                                               :> MultiVerb
                                                                                                                                    'GET
                                                                                                                                    '[JSON]
                                                                                                                                    '[Respond
                                                                                                                                        404
                                                                                                                                        "Not blacklisted"
                                                                                                                                        (),
                                                                                                                                      Respond
                                                                                                                                        200
                                                                                                                                        "Yes blacklisted"
                                                                                                                                        ()]
                                                                                                                                    CheckBlacklistResponse)))
                                                                                                                    :<|> (Named
                                                                                                                            "iDeleteBlacklist"
                                                                                                                            ("users"
                                                                                                                             :> ("blacklist"
                                                                                                                                 :> (QueryParam'
                                                                                                                                       '[Required,
                                                                                                                                         Strict]
                                                                                                                                       "email"
                                                                                                                                       EmailAddress
                                                                                                                                     :> Delete
                                                                                                                                          '[JSON]
                                                                                                                                          NoContent)))
                                                                                                                          :<|> (Named
                                                                                                                                  "iPostBlacklist"
                                                                                                                                  ("users"
                                                                                                                                   :> ("blacklist"
                                                                                                                                       :> (QueryParam'
                                                                                                                                             '[Required,
                                                                                                                                               Strict]
                                                                                                                                             "email"
                                                                                                                                             EmailAddress
                                                                                                                                           :> Post
                                                                                                                                                '[JSON]
                                                                                                                                                NoContent)))
                                                                                                                                :<|> (Named
                                                                                                                                        "iPutUserSsoId"
                                                                                                                                        ("users"
                                                                                                                                         :> (Capture
                                                                                                                                               "uid"
                                                                                                                                               UserId
                                                                                                                                             :> ("sso-id"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       UserSSOId
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[RespondEmpty
                                                                                                                                                              200
                                                                                                                                                              "UpdateSSOIdSuccess",
                                                                                                                                                            RespondEmpty
                                                                                                                                                              404
                                                                                                                                                              "UpdateSSOIdNotFound"]
                                                                                                                                                          UpdateSSOIdResponse))))
                                                                                                                                      :<|> (Named
                                                                                                                                              "iDeleteUserSsoId"
                                                                                                                                              ("users"
                                                                                                                                               :> (Capture
                                                                                                                                                     "uid"
                                                                                                                                                     UserId
                                                                                                                                                   :> ("sso-id"
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'DELETE
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "UpdateSSOIdSuccess",
                                                                                                                                                              RespondEmpty
                                                                                                                                                                404
                                                                                                                                                                "UpdateSSOIdNotFound"]
                                                                                                                                                            UpdateSSOIdResponse)))
                                                                                                                                            :<|> (Named
                                                                                                                                                    "iPutManagedBy"
                                                                                                                                                    ("users"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "uid"
                                                                                                                                                           UserId
                                                                                                                                                         :> ("managed-by"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ManagedByUpdate
                                                                                                                                                                 :> Put
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      NoContent))))
                                                                                                                                                  :<|> (Named
                                                                                                                                                          "iPutRichInfo"
                                                                                                                                                          ("users"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "uid"
                                                                                                                                                                 UserId
                                                                                                                                                               :> ("rich-info"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         RichInfoUpdate
                                                                                                                                                                       :> Put
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            NoContent))))
                                                                                                                                                        :<|> (Named
                                                                                                                                                                "iPutHandle"
                                                                                                                                                                ("users"
                                                                                                                                                                 :> (Capture
                                                                                                                                                                       "uid"
                                                                                                                                                                       UserId
                                                                                                                                                                     :> ("handle"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               HandleUpdate
                                                                                                                                                                             :> Put
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  NoContent))))
                                                                                                                                                              :<|> (Named
                                                                                                                                                                      "iPutUserName"
                                                                                                                                                                      ("users"
                                                                                                                                                                       :> (Capture
                                                                                                                                                                             "uid"
                                                                                                                                                                             UserId
                                                                                                                                                                           :> ("name"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     NameUpdate
                                                                                                                                                                                   :> Put
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        NoContent))))
                                                                                                                                                                    :<|> (Named
                                                                                                                                                                            "iGetRichInfo"
                                                                                                                                                                            ("users"
                                                                                                                                                                             :> (Capture
                                                                                                                                                                                   "uid"
                                                                                                                                                                                   UserId
                                                                                                                                                                                 :> ("rich-info"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          RichInfo)))
                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                  "iGetRichInfoMulti"
                                                                                                                                                                                  ("users"
                                                                                                                                                                                   :> ("rich-info"
                                                                                                                                                                                       :> (QueryParam'
                                                                                                                                                                                             '[Optional,
                                                                                                                                                                                               Strict]
                                                                                                                                                                                             "ids"
                                                                                                                                                                                             (CommaSeparatedList
                                                                                                                                                                                                UserId)
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                [(UserId,
                                                                                                                                                                                                  RichInfo)])))
                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                        "iHeadHandle"
                                                                                                                                                                                        (CanThrow
                                                                                                                                                                                           'InvalidHandle
                                                                                                                                                                                         :> ("users"
                                                                                                                                                                                             :> ("handles"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "handle"
                                                                                                                                                                                                       Handle
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'HEAD
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "CheckHandleResponseFound",
                                                                                                                                                                                                            RespondEmpty
                                                                                                                                                                                                              404
                                                                                                                                                                                                              "CheckHandleResponseNotFound"]
                                                                                                                                                                                                          CheckHandleResponse))))
                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                              "iConnectionUpdate"
                                                                                                                                                                                              ("connections"
                                                                                                                                                                                               :> ("connection-update"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         UpdateConnectionsInternal
                                                                                                                                                                                                       :> Put
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            NoContent)))
                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                    "iListClients"
                                                                                                                                                                                                    ("clients"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           UserSet
                                                                                                                                                                                                         :> Post
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              UserClients))
                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                          "iListClientsFull"
                                                                                                                                                                                                          ("clients"
                                                                                                                                                                                                           :> ("full"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     UserSet
                                                                                                                                                                                                                   :> Post
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        UserClientsFull)))
                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                "iAddClient"
                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                   "This endpoint can lead to the following events being sent: ClientAdded event to the user; ClientRemoved event to the user, if removing old clients due to max number of clients; UserLegalHoldEnabled event to contacts of the user, if client type is legalhold."
                                                                                                                                                                                                                 :> ("clients"
                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                           "uid"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> (QueryParam'
                                                                                                                                                                                                                               '[Optional,
                                                                                                                                                                                                                                 Strict]
                                                                                                                                                                                                                               "skip_reauth"
                                                                                                                                                                                                                               Bool
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   NewClient
                                                                                                                                                                                                                                 :> (Header'
                                                                                                                                                                                                                                       '[Optional,
                                                                                                                                                                                                                                         Strict]
                                                                                                                                                                                                                                       "Z-Connection"
                                                                                                                                                                                                                                       ConnId
                                                                                                                                                                                                                                     :> Verb
                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                          201
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          Client))))))
                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                      "iLegalholdAddClient"
                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                         "This endpoint can lead to the following events being sent: LegalHoldClientRequested event to contacts of the user"
                                                                                                                                                                                                                       :> ("clients"
                                                                                                                                                                                                                           :> ("legalhold"
                                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                                     "uid"
                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                   :> ("request"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             LegalHoldClientRequest
                                                                                                                                                                                                                                           :> Post
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                NoContent))))))
                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                           "iLegalholdDeleteClient"
                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                              "This endpoint can lead to the following events being sent: ClientRemoved event to the user; UserLegalHoldDisabled event to contacts of the user"
                                                                                                                                                                                                                            :> ("clients"
                                                                                                                                                                                                                                :> ("legalhold"
                                                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                                                          "uid"
                                                                                                                                                                                                                                          UserId
                                                                                                                                                                                                                                        :> Delete
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             NoContent)))))))))))))))))))))))))))))))))))))
                   :<|> (("mls"
                          :> (Summary
                                "Return all clients and all MLS-capable clients of a user"
                              :> ("clients"
                                  :> (CanThrow 'UserNotFound
                                      :> (Capture "user" UserId
                                          :> (QueryParam'
                                                '[Required, Strict] "ciphersuite" CipherSuite
                                              :> MultiVerb
                                                   'GET
                                                   '[JSON]
                                                   '[Respond 200 "MLS clients" (Set ClientInfo)]
                                                   (Set ClientInfo)))))))
                         :<|> (GetVerificationCode
                               :<|> (TeamsAPI
                                     :<|> ((UpdateUserLocale
                                            :<|> (DeleteUserLocale
                                                  :<|> (GetDefaultLocale
                                                        :<|> Named
                                                               "get-user-export-data"
                                                               (Summary "Get user export data"
                                                                :> ("users"
                                                                    :> (Capture "uid" UserId
                                                                        :> ("export-data"
                                                                            :> MultiVerb
                                                                                 'GET
                                                                                 '[JSON]
                                                                                 '[Respond
                                                                                     200
                                                                                     "User export data"
                                                                                     (Maybe
                                                                                        TeamExportUser)]
                                                                                 (Maybe
                                                                                    TeamExportUser))))))))
                                           :<|> (Named
                                                   "update-client-last-active"
                                                   (Summary "Update last_active field of a client"
                                                    :> ("clients"
                                                        :> (Capture "uid" UserId
                                                            :> (Capture "client" ClientId
                                                                :> ("activity"
                                                                    :> MultiVerb
                                                                         'POST
                                                                         '[JSON]
                                                                         '[RespondEmpty 200 "OK"]
                                                                         ())))))
                                                 :<|> ((Named
                                                          "legalhold-login"
                                                          ("legalhold-login"
                                                           :> (ReqBody '[JSON] LegalHoldLogin
                                                               :> MultiVerb
                                                                    'POST
                                                                    '[JSON]
                                                                    '[TokenResponse]
                                                                    (AccessWithCookie
                                                                       UserTokenCookie)))
                                                        :<|> (Named
                                                                "sso-login"
                                                                ("sso-login"
                                                                 :> (ReqBody '[JSON] SsoLogin
                                                                     :> (QueryParam'
                                                                           '[Optional, Strict]
                                                                           "persist"
                                                                           Bool
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[TokenResponse]
                                                                              (AccessWithCookie
                                                                                 UserTokenCookie))))
                                                              :<|> (Named
                                                                      "login-code"
                                                                      ("users"
                                                                       :> ("login-code"
                                                                           :> (QueryParam'
                                                                                 '[Required, Strict]
                                                                                 "phone"
                                                                                 Phone
                                                                               :> MultiVerb
                                                                                    'GET
                                                                                    '[JSON]
                                                                                    '[Respond
                                                                                        200
                                                                                        "Login code"
                                                                                        PendingLoginCode]
                                                                                    PendingLoginCode)))
                                                                    :<|> Named
                                                                           "reauthenticate"
                                                                           ("users"
                                                                            :> (Capture "uid" UserId
                                                                                :> ("reauthenticate"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          ReAuthUser
                                                                                        :> MultiVerb
                                                                                             'GET
                                                                                             '[JSON]
                                                                                             '[RespondEmpty
                                                                                                 200
                                                                                                 "OK"]
                                                                                             ())))))))
                                                       :<|> (OAuthAPI
                                                             :<|> (ISearchIndexAPI
                                                                   :<|> (FederationRemotesAPI
                                                                         :<|> Named
                                                                                "get-provider-activation-code"
                                                                                (Summary
                                                                                   "Retrieve activation code via api instead of email (for testing only)"
                                                                                 :> ("provider"
                                                                                     :> ("activation-code"
                                                                                         :> (QueryParam'
                                                                                               '[Required,
                                                                                                 Strict]
                                                                                               "email"
                                                                                               EmailAddress
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[Respond
                                                                                                      200
                                                                                                      ""
                                                                                                      KeyValuePair]
                                                                                                  KeyValuePair)))))))))))))))))
-> OpenApi
forall {k} (api :: k). HasOpenApi api => Proxy api -> OpenApi
toOpenApi (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @API)
      OpenApi -> (OpenApi -> OpenApi) -> OpenApi
forall a b. a -> (a -> b) -> b
& (Info -> Identity Info) -> OpenApi -> Identity OpenApi
forall s a. HasInfo s a => Lens' s a
Lens' OpenApi Info
info ((Info -> Identity Info) -> OpenApi -> Identity OpenApi)
-> ((Text -> Identity Text) -> Info -> Identity Info)
-> (Text -> Identity Text)
-> OpenApi
-> Identity OpenApi
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> Info -> Identity Info
forall s a. HasTitle s a => Lens' s a
Lens' Info Text
title ((Text -> Identity Text) -> OpenApi -> Identity OpenApi)
-> Text -> OpenApi -> OpenApi
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"Wire-Server internal brig API"
  )

newtype BrigInternalClient a = BrigInternalClient (Servant.ClientM a)
  deriving newtype ((forall a b.
 (a -> b) -> BrigInternalClient a -> BrigInternalClient b)
-> (forall a b. a -> BrigInternalClient b -> BrigInternalClient a)
-> Functor BrigInternalClient
forall a b. a -> BrigInternalClient b -> BrigInternalClient a
forall a b.
(a -> b) -> BrigInternalClient a -> BrigInternalClient b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> BrigInternalClient a -> BrigInternalClient b
fmap :: forall a b.
(a -> b) -> BrigInternalClient a -> BrigInternalClient b
$c<$ :: forall a b. a -> BrigInternalClient b -> BrigInternalClient a
<$ :: forall a b. a -> BrigInternalClient b -> BrigInternalClient a
Functor, Functor BrigInternalClient
Functor BrigInternalClient =>
(forall a. a -> BrigInternalClient a)
-> (forall a b.
    BrigInternalClient (a -> b)
    -> BrigInternalClient a -> BrigInternalClient b)
-> (forall a b c.
    (a -> b -> c)
    -> BrigInternalClient a
    -> BrigInternalClient b
    -> BrigInternalClient c)
-> (forall a b.
    BrigInternalClient a
    -> BrigInternalClient b -> BrigInternalClient b)
-> (forall a b.
    BrigInternalClient a
    -> BrigInternalClient b -> BrigInternalClient a)
-> Applicative BrigInternalClient
forall a. a -> BrigInternalClient a
forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient a
forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient b
forall a b.
BrigInternalClient (a -> b)
-> BrigInternalClient a -> BrigInternalClient b
forall a b c.
(a -> b -> c)
-> BrigInternalClient a
-> BrigInternalClient b
-> BrigInternalClient c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall a. a -> BrigInternalClient a
pure :: forall a. a -> BrigInternalClient a
$c<*> :: forall a b.
BrigInternalClient (a -> b)
-> BrigInternalClient a -> BrigInternalClient b
<*> :: forall a b.
BrigInternalClient (a -> b)
-> BrigInternalClient a -> BrigInternalClient b
$cliftA2 :: forall a b c.
(a -> b -> c)
-> BrigInternalClient a
-> BrigInternalClient b
-> BrigInternalClient c
liftA2 :: forall a b c.
(a -> b -> c)
-> BrigInternalClient a
-> BrigInternalClient b
-> BrigInternalClient c
$c*> :: forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient b
*> :: forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient b
$c<* :: forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient a
<* :: forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient a
Applicative, Applicative BrigInternalClient
Applicative BrigInternalClient =>
(forall a b.
 BrigInternalClient a
 -> (a -> BrigInternalClient b) -> BrigInternalClient b)
-> (forall a b.
    BrigInternalClient a
    -> BrigInternalClient b -> BrigInternalClient b)
-> (forall a. a -> BrigInternalClient a)
-> Monad BrigInternalClient
forall a. a -> BrigInternalClient a
forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient b
forall a b.
BrigInternalClient a
-> (a -> BrigInternalClient b) -> BrigInternalClient b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall a b.
BrigInternalClient a
-> (a -> BrigInternalClient b) -> BrigInternalClient b
>>= :: forall a b.
BrigInternalClient a
-> (a -> BrigInternalClient b) -> BrigInternalClient b
$c>> :: forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient b
>> :: forall a b.
BrigInternalClient a
-> BrigInternalClient b -> BrigInternalClient b
$creturn :: forall a. a -> BrigInternalClient a
return :: forall a. a -> BrigInternalClient a
Monad, Monad BrigInternalClient
Monad BrigInternalClient =>
(Maybe [Status] -> Request -> BrigInternalClient Response)
-> (forall a. ClientError -> BrigInternalClient a)
-> RunClient BrigInternalClient
Maybe [Status] -> Request -> BrigInternalClient Response
forall a. ClientError -> BrigInternalClient a
forall (m :: * -> *).
Monad m =>
(Maybe [Status] -> Request -> m Response)
-> (forall a. ClientError -> m a) -> RunClient m
$crunRequestAcceptStatus :: Maybe [Status] -> Request -> BrigInternalClient Response
runRequestAcceptStatus :: Maybe [Status] -> Request -> BrigInternalClient Response
$cthrowClientError :: forall a. ClientError -> BrigInternalClient a
throwClientError :: forall a. ClientError -> BrigInternalClient a
Servant.RunClient)

brigInternalClient :: forall (name :: Symbol) endpoint. (HasEndpoint API endpoint name, Servant.HasClient BrigInternalClient endpoint) => Servant.Client BrigInternalClient endpoint
brigInternalClient :: forall (name :: Symbol) endpoint.
(HasEndpoint API endpoint name,
 HasClient BrigInternalClient endpoint) =>
Client BrigInternalClient endpoint
brigInternalClient = forall api (name :: Symbol) (m :: * -> *) endpoint.
(HasEndpoint api endpoint name, HasClient m endpoint) =>
Client m endpoint
namedClient @API @name @BrigInternalClient

runBrigInternalClient :: HTTP.Manager -> Endpoint -> BrigInternalClient a -> IO (Either Servant.ClientError a)
runBrigInternalClient :: forall a.
Manager
-> Endpoint -> BrigInternalClient a -> IO (Either ClientError a)
runBrigInternalClient Manager
httpMgr (Endpoint Text
brigHost Word16
brigPort) (BrigInternalClient ClientM a
action) = do
  let baseUrl :: BaseUrl
baseUrl = Scheme -> String -> Int -> String -> BaseUrl
Servant.BaseUrl Scheme
Servant.Http (Text -> String
Text.unpack Text
brigHost) (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
brigPort) String
""
      clientEnv :: ClientEnv
clientEnv = Manager
-> BaseUrl
-> Maybe (TVar CookieJar)
-> (BaseUrl -> Request -> IO Request)
-> ClientEnv
Servant.ClientEnv Manager
httpMgr BaseUrl
baseUrl Maybe (TVar CookieJar)
forall a. Maybe a
Nothing BaseUrl -> Request -> IO Request
Servant.defaultMakeClientRequest
  ClientM a -> ClientEnv -> IO (Either ClientError a)
forall a. ClientM a -> ClientEnv -> IO (Either ClientError a)
Servant.runClientM ClientM a
action ClientEnv
clientEnv